home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
IRIX 6.2 Development Libraries
/
SGI IRIX 6.2 Development Libraries.iso
/
dist
/
complib.idb
/
usr
/
share
/
catman
/
p_man
/
cat3
/
complib
/
CCHUD.z
/
CCHUD
Wrap
Text File
|
1996-03-14
|
4KB
|
133 lines
CCCCCCCCHHHHUUUUDDDD((((3333FFFF)))) CCCCCCCCHHHHUUUUDDDD((((3333FFFF))))
NNNNAAAAMMMMEEEE
CCHUD - CCHUD updates an augmented Cholesky decomposition of the
triangular part of an augmented QR decomposition. Specifically, given an
upper triangular matrix R of order P, a row vector X, a column vector Z,
and a scalar Y, CCHUD determines a unitary matrix U and a scalar ZETA
such that
(R Z) (RR ZZ )
U * ( ) = ( ) ,
(X Y) ( 0 ZETA)
where RR is upper triangular. If R and Z have been obtained from the
factorization of a least squares problem, then RR and ZZ are the factors
corresponding to the problem with the observation (X,Y) appended. In
this case, if RHO is the norm of the residual vector, then the norm of
the residual vector of the updated problem is SQRT(RHO**2 + ZETA**2).
CCHUD will simultaneously update several triplets (Z,Y,RHO).
For a less terse description of what CCHUD does and how it may be applied
see the LINPACK Guide.
The matrix U is determined as the product U(P)*...*U(1), where U(I) is a
rotation in the (I,P+1) plane of the form
( (CI) S(I) )
( ) .
( -CONJG(S(I)) (CI) )
The rotations are chosen so that C(I) is real.
SSSSYYYYNNNNOOOOPPPPSSSSYYYYSSSS
SUBROUTINE CCHUD(R,LDR,P,X,Z,LDZ,NZ,Y,RHO,C,S)
DDDDEEEESSSSCCCCRRRRIIIIPPPPTTTTIIIIOOOONNNN
On Entry
RRRR COMPLEX(LDR,P), where LDR .GE. P.
R contains the upper triangular matrix
that is to be updated. The part of R
below the diagonal is not referenced.
LLLLDDDDRRRR INTEGER.
LDR is the leading dimension of the array R.
PPPP INTEGER.
P is the order of the matrix R.
XXXX COMPLEX(P).
X contains the row to be added to R. X is
not altered by CCHUD.
PPPPaaaaggggeeee 1111
CCCCCCCCHHHHUUUUDDDD((((3333FFFF)))) CCCCCCCCHHHHUUUUDDDD((((3333FFFF))))
ZZZZ COMPLEX(LDZ,NZ), where LDZ .GE. P.
Z is an array containing NZ P-vectors to
be updated with R.
LLLLDDDDZZZZ INTEGER.
LDZ is the leading dimension of the array Z.
NNNNZZZZ INTEGER.
NZ is the number of vectors to be updated
NZ may be zero, in which case Z, Y, and RHO
are not referenced.
YYYY COMPLEX(NZ).
Y contains the scalars for updating the vectors
Z. Y is not altered bY CCHUD.
RRRRHHHHOOOO REAL(NZ).
RHO contains the norms of the residual
vectors that are to be updated. If RHO(J)
is negative, it is left unaltered. On Return RC
RRRRHHHHOOOO contain the updated quantities.
ZZZZ
CCCC REAL(P).
C contains the cosines of the transforming
rotations.
SSSS COMPLEX(P).
S contains the sines of the transforming
rotations. LINPACK. This version dated 08/14/78 . Stewart, G. W.,
University of Maryland, Argonne National Lab.
CCCCCCCCHHHHUUUUDDDD uses the following functions and subroutines. Extended BLAS CROTG
Fortran CONJG,SQRT
PPPPaaaaggggeeee 2222